Throughfall Subroutine

public subroutine Throughfall(rain, lai, domain, fv, raineff)

calculate the effective rainfall through canopy

Arguments

Type IntentOptional Attributes Name
type(grid_real), intent(in) :: rain

rainfall rate (m/s)

type(grid_real), intent(in) :: lai

leaf area index (m2/m2)

type(grid_integer), intent(in) :: domain

analysis domain

type(grid_real), intent(in) :: fv

fraction of vegetation covering the cell (0-1)

type(grid_real), intent(inout) :: raineff

effecttive rainfall rate (throughfall) (m/s)


Variables

Type Visibility Attributes Name Initial
real(kind=float), public :: canopyinter

is the amount of water intercepted at current time step

real(kind=float), public :: canopymaxi

maximum canopy storage at current day's leaf area index

integer(kind=short), public :: i
integer(kind=short), public :: j
real(kind=float), public :: raindt

rainfall amount in the given dt (mm)


Source Code

SUBROUTINE Throughfall &
!
(rain , lai, domain, fv, raineff)
   
 IMPLICIT NONE 

!Arguments with intent in
TYPE (grid_real), INTENT(IN) :: rain !!rainfall rate (m/s)
TYPE (grid_real), INTENT(IN) :: lai   !!leaf area index (m2/m2)
TYPE (grid_integer), INTENT(IN) :: domain !!analysis domain
TYPE (grid_real), INTENT(IN) :: fv !!fraction of vegetation covering the cell (0-1)

!arguments with intent inout
TYPE (grid_real), INTENT(INOUT) :: raineff  !!effecttive rainfall rate (throughfall) (m/s)

!local declarations:

REAL (KIND = float) :: canopyinter   !! is the amount of water intercepted at current time step
REAL (KIND = float) :: canopymaxi  !! maximum canopy storage at current day's leaf area index
REAL (KIND = float) :: raindt !!rainfall amount in the given dt (mm)
INTEGER (KIND = short) :: i, j
!-------------------------end of declarations----------------------------------


DO j = 1, domain % jdim
    DO i = 1, domain % idim
        IF (domain % mat (i,j) /= domain % nodata ) THEN
    
            !compute maximum amount of water that can be held in canopy  storage as a function of lai
            canopymaxi = canopymax % mat (i,j) * lai % mat (i,j) / laimax % mat (i,j) / millimeter ! unit = mm

            !compute amount of rainfall of the given dt in mm, before canopy interception is removed
            raindt = rain % mat (i,j) * dtCanopyInterception / millimeter

            !update amount of intercepted rainfall. The canopy storage is filled before any 
            ! water is allowed to reach the ground
            IF ( raindt <= canopymaxi - canopyStorage % mat (i,j) ) THEN !rain is lower than the available storage
                canopyStorage % mat (i,j) = canopyStorage % mat (i,j) + raindt  !all rain is intercepted
                raineff % mat (i,j) = 0.
            ELSE !rain amount is greater than available storage
                raineff % mat (i,j) = raindt - ( canopymaxi - canopyStorage % mat (i,j) )
                canopyStorage % mat (i,j) = canopymaxi !canopy storage reaches maximum value
    
            END IF
 
            !convert raineff from mm to m/s
            raineff % mat (i,j) = raineff % mat (i,j) * millimeter / dtCanopyInterception
            
            !canopy affects only fraction of ground surface covered by vegetation,
            !adjust raineff for bare soil
            raineff % mat (i,j) = fv % mat (i,j) * raineff % mat (i,j) + &
                                  ( 1. - fv % mat (i,j) ) * rain % mat (i,j)
            
           
        END IF
   END DO
END DO

RETURN

END SUBROUTINE Throughfall